SCScurveNumber Function

public function SCScurveNumber(rain, raincum, c, s, dt, runoff) result(inf)

calculates the actual rate of infiltration (m/s) according to Curve Number model modified for continuous simulation

References:

Ravazzani, G., Mancini, M., Giudici, I., & Amadio, P.. (2007). Effects of soil moisture parameterization on a real- time flood forecasting system based on rainfall thresholds. IAHS publication, 313, 407–416.

Rabuffetti, D., Ravazzani, G., Corbari, C., & Mancini, M.. (2008). Verification of operational quantitative discharge forecast (QDF) for a regional warning system – the AMPHORE case studies in the upper Po river. Natural hazards and earth system sciences, 8, 161–173.

Ravazzani, G., Amengual, A., Ceppi, A., Homar, V., Romero, R., Lombardi, G., & Mancini, M.. (2016). Potentialities of ensemble strategies for flood forecasting over the Milano urban area. Journal of hydrology, 539, 237-253.

Arguments

Type IntentOptional Attributes Name
real(kind=float), intent(in) :: rain

rainfall rate (m/s)

real(kind=float), intent(inout) :: raincum

cumulated rainfall from start of storm (mm) is used and updated to be ready for the following step

real(kind=float), intent(in) :: c

initial abstraction ratio (-)

real(kind=float), intent(in) :: s

soil retention capacity (mm)

integer(kind=short), intent(in) :: dt

time step (s)

real(kind=double), intent(out) :: runoff

runoff rate (m/s)

Return Value real(kind=float)

infiltration rate (m/s)


Variables

Type Visibility Attributes Name Initial
real(kind=float), public :: raincump

cumulative precipitation of previous time step (mm)

real(kind=float), public :: runoffp

cumulative runoff of previous time step (mm)


Source Code

FUNCTION SCScurveNumber &
!
(rain, raincum, c, s, dt, runoff) &
!
RESULT (inf)


IMPLICIT NONE

!Arguments with intent in
REAL (KIND = float), INTENT(IN) :: rain !!rainfall rate (m/s)
REAL (KIND = float), INTENT(IN) :: c !!initial abstraction ratio (-)
REAL (KIND = float), INTENT(IN) :: s !!soil retention capacity (mm)
INTEGER (KIND = short), INTENT(IN) :: dt !!time step (s)

!Arguments with intent inout:
REAL (KIND = float), INTENT(INOUT) :: raincum !!cumulated rainfall from start of storm (mm)
                                              !! is used and updated to be ready for the 
                                              !! following step

!Arguments with intent out
REAL (KIND = double),  INTENT(OUT) :: runoff !!runoff rate (m/s)

!local declarations:
REAL (KIND = float) :: inf !!infiltration rate (m/s)
REAL (KIND = float) :: raincump  !!cumulative precipitation of previous time step (mm)
REAL (KIND = float) :: runoffp  !!cumulative runoff of previous time step (mm)


!-------------------------end of declarations----------------------------------
!if retention capacity = 0 (soil is saturated)
! rainfall is transformed to runoff 
IF (s == 0.) THEN
		raincum = raincum + rain * 1000. * dt !update cumulative rainfall
		runoff = rain
		inf = 0.
		RETURN !no need to continue
END IF

!calculate runoff and infiltration rate  

!update cumulative precipitation
raincump = raincum !save cumulated precipitation amount of previous time step
raincum = raincum + rain * dt * 1000. !(mm)
  
!runoff at current time
IF(raincum >= c*s) THEN
	runoff = ((raincum - c*s )**2.) / (raincum + (1.-c) * s)
ELSE
	runoff = 0.
END IF
     
!runoff at previous time
IF(raincump >= c*S) THEN
	runoffp = ((raincump - c*S )**2.) / (raincump + (1.-c) * s)
ELSE
	runoffp = 0.
END IF
    
!actual runoff in m/s
runoff = (runoff - runoffp) / 1000. / dt
    
!actual infiltration rate in m/s
inf = rain - runoff

RETURN
END FUNCTION SCScurveNumber